PrecipitationInit Subroutine

public subroutine PrecipitationInit(ini, mask, dtMeteo, tstart, dem_loaded)

Initialize precipitation

Arguments

Type IntentOptional Attributes Name
type(IniList), intent(in) :: ini
type(grid_integer), intent(in) :: mask

defines interpolation extent

integer(kind=short), intent(in) :: dtMeteo

deltat of meteo data reading

type(DateTime), intent(in) :: tstart

initial time

logical, intent(in) :: dem_loaded

true if dem has been loaded


Variables

Type Visibility Attributes Name Initial
character(len=1000), public :: filename
type(DateTime), public :: lapseTime
type(grid_real), public :: meteoTemp

Source Code

SUBROUTINE PrecipitationInit &
!
( ini, mask, dtMeteo, tstart, dem_loaded )

IMPLICIT NONE

TYPE (IniList), INTENT(IN) :: ini
TYPE (grid_integer), INTENT(IN) :: mask  !!defines interpolation extent
INTEGER (KIND = short), INTENT(IN) :: dtMeteo !! deltat of meteo data reading
TYPE (DateTime),     INTENT(IN) :: tstart !!initial time
LOGICAL , INTENT (in) :: dem_loaded !! true if dem has been loaded


!local declarations
CHARACTER (LEN = 1000) :: filename
TYPE (DateTime) :: lapseTime
TYPE (grid_real) :: meteoTemp


!-------------------------end of declarations----------------------------------
!set initial time
  timeNew = tstart  

  !initialize grid
  CALL NewGrid (precipitationRate, mask, 0.)
  CALL NewGrid (grid_devst, mask, 0.)
  
  !set deltat
  dtPrecipitation = IniReadInt ('dt', ini, section = 'precipitation')

	!check dtPrecipitation is multiple of dtMeteo
  IF (.NOT.(MOD(dtPrecipitation,dtMeteo) == 0)) THEN
           CALL Catch ('error', 'Precipitation',   &
		                 'dt is not multiple of dtMeteo')
  END IF
  
  !set valid threshold
  IF (KeyIsPresent ('valid-threshold', ini, &
                         section = 'precipitation') ) THEN
      valid_prcn = IniReadReal ('valid-threshold', ini, &
                                        section = 'precipitation')
  ELSE ! set to default = 1.0 
      CALL Catch ('info', 'Precipitation',   &
		                 'valid-threshold not defined, set to 1')
      valid_prcn = 1.
  END IF

  !set cell-size
  cellsizeInterpolation = mask % cellsize
  
  !interpolation-assignment method
  IF (KeyIsPresent('interpolation-assignment', ini, &
                     section = 'precipitation') ) THEN
      interpolationMethod_assignment = IniReadInt ('interpolation-assignment', ini, &
                                    section = 'precipitation')
  ELSE
    CALL Catch ('error', 'Precipitation',   &
                'interpolation-assignment missing in meteo configuration file')
  END IF   


  !set interpolation method
  IF (interpolationMethod_assignment == 1) THEN

      interpolationMethod = IniReadInt ('interpolation', ini, &
                                    section = 'precipitation')
      
	    CALL SetSpecificProperties (interpolationMethod, ini, mask)
  
  ELSE !read map
      interpolationMethod = -1
      CALL GridByIni (ini, interpolationMethod_map, "precipitation", &
                     "interpolation")
      !scan for interpolation methods included
      interpolationMethod_vector = 0
      DO i = 1, interpolationMethod_map % idim
        DO j = 1, interpolationMethod_map % jdim
            IF (interpolationMethod_map % mat(i,j) /= &
                interpolationMethod_map % nodata) THEN
                interpolationMethod_vector &
                   (interpolationMethod_map % mat (i,j)) = &
                    interpolationMethod_map % mat (i,j)
            END IF
        END DO
      END DO

      DO i = 1, 3
         CALL SetSpecificProperties (interpolationMethod_vector (i), ini, mask)
      END DO

  END IF

  !scale factor and offset
	IF (KeyIsPresent('offset', ini, section = 'precipitation')) THEN	
	   offset_value = IniReadReal ('offset', ini, section = 'precipitation')
	ELSE
	    offset_value = MISSING_DEF_REAL
	END IF
	
	IF (KeyIsPresent('scale-factor', ini, section = 'precipitation')) THEN	
	   scale_factor = IniReadReal ('scale-factor', ini, section = 'precipitation')
	ELSE
	    scale_factor = MISSING_DEF_REAL
	END IF			

  !set power_idw
  IF (KeyIsPresent('idw-power', ini, section = 'precipitation')) THEN	
	   idw_power = IniReadReal ('idw-power', ini, section = 'precipitation')
	ELSE !set default value
	    idw_power = 2.
	END IF	
 
	!file
  filename = IniReadString ('file', ini, section = 'precipitation')
    IF (interpolationMethod_assignment == 1 .AND. &
        interpolationMethod == 0) THEN !data are stored in net-cdf file
       !store net-cdf filename
       fileGrid = filename
       IF ( KeyIsPresent ('variable', ini, section = 'precipitation') ) THEN
          precipitationRate % var_name = IniReadString ('variable', &
                                             ini, section = 'precipitation')
            !read grid and store as temporary file
             CALL NewGrid (layer = meteoTemp, fileName = TRIM(fileGrid), &
                         fileFormat = NET_CDF, &
                         variable = TRIM(precipitationRate % var_name) )
       ELSE IF  (KeyIsPresent ('standard_name', ini, &
                              section = 'precipitation') ) THEN
          precipitationRate % standard_name = IniReadString ('standard_name', &
                                              ini, section = 'precipitation')
       ELSE
          CALL Catch ('error', 'Precipitation',   &
		       'standard_name or variable missing in section precipitation' )
       END IF      

       !set cellsize to zero. Optimal cellsize is automatically computed
       cellsizeInterpolation = 0.
            
    ELSE !open file containing local measurements
       fileunit = GetUnit ()
	     OPEN(fileunit,file = filename(1:LEN_TRIM(filename)),status='old')
    END IF
    
  !use elevation to modify precipitation
  IF ( KeyIsPresent ('elevation-drift', ini, section = 'precipitation') ) THEN
	     elevationDrift = IniReadInt ('elevation-drift', ini, section = 'precipitation')
  ELSE
      elevationDrift = 0 !default, suppress drift
  END IF
  
  IF (elevationDrift == 1) THEN
      
      IF (interpolationMethod == 0 ) THEN
            CALL Catch ('error', 'Precipitation',   &
                'elevation drift cannot be applied when interpolation = 0 ')
       END IF
      
      !check if dem have been loaded by domain properties
      IF ( .NOT. dem_loaded) THEN
           CALL Catch ('error', 'Precipitation',   &
                        'dem for elevation drift was not loaded ')
      END IF
        
      !set lapse rate assignment
       IF (KeyIsPresent ('lapse-rate-assignment', ini, &
                         section = 'precipitation') )  THEN
           lapse_rate_assignment = IniReadInt ('lapse-rate-assignment', ini, &
                                        section = 'precipitation')
       ELSE !lapse-rate-assignment missing
           CALL Catch ('error', 'Precipitation',   &
		                 'lapse-rate-assignment missing in meteo configuration file')
       END IF
       
      !lapse rate map
       IF (lapse_rate_assignment == 2) THEN
           IF ( SubSectionIsPresent (subsection = 'lapse-rate-map', &
                    section = 'precipitation', iniDb = ini) ) THEN

              !check all keywords are defined
              IF (IniReadString ('format', ini, 'precipitation',&
                                       'lapse-rate-map') == 'net-cdf') THEN

                   IF (KeyIsPresent ('time',ini, 'precipitation', &
                                                   'lapse-rate-map'))  THEN
                       timeString = IniReadString ('time', ini, &
                                'precipitation', 'lapse-rate-map') 
                       lapseTime = timeString 
                       IF (lapseTime > tstart) THEN
                           CALL Catch ('error', 'Precipitation',   &
		                    'lapse-rate-map time greater than starting time' )
                       END IF
                   ELSE
                        CALL Catch ('error', 'Precipitation',   &
		                    'time keyword is missing in lapse-rate-map subsection' )
                   END IF

              END IF
              
              CALL GridByIni (ini, lapse_map, "precipitation", "lapse-rate-map") 
              !check coordinate reference system and spatial resolution
             IF (.NOT. CRSisEqual (mask = mask, grid = lapse_map, &
                                   checkCells= .TRUE.)) THEN
                  CALL Catch ('error', 'Precipitation',   &
		                 'wrong lapse-rate-map spatial reference system ')
             END IF
           ELSE
              CALL Catch ('error', 'Precipitation',   &
		                 'lapse-rate-map missing in meteo configuration file')
           END IF
       ELSE !build lapse map from scalar value

           IF ( KeyIsPresent ('lapse-rate-scalar', ini, &
                    section = 'precipitation') ) THEN
                lapse = IniReadReal ('lapse-rate-scalar', ini, &
                   section = 'precipitation')
                CALL NewGrid (lapse_map, mask)
                lapse_map = lapse / 3600. !convert lapse rate from mm/h/m to mm/s/m
           ELSE
                CALL Catch ('error', 'Precipitation',   &
		                 'lapse-rate-scalar missing in meteo configuration file')
           END IF
           
       END IF  !lapse_rate_assignment  	
  END IF !elevationDrift 

  !grid exporting settings
  IF (KeyIsPresent ('export', ini, section = 'precipitation')  )  THEN
     export = IniReadInt ('export', ini, section = 'precipitation')
  ELSE
     export = 0
  END IF 

  IF (export == 1) THEN
     
     !set export path name
     IF (KeyIsPresent ('export-path', ini, section = 'precipitation')  )  THEN
         export_path = IniReadString ('export-path', ini, section = 'precipitation')
         !check if path ends with / or \
         IF (  export_path (LEN_TRIM (export_path):LEN_TRIM (export_path)) /= '\' .AND. &
               export_path (LEN_TRIM (export_path):LEN_TRIM (export_path)) /= '/' ) THEN
             export_path (LEN_TRIM (export_path)+1:LEN_TRIM (export_path)+1) = '\'
         END IF
       
         IF (INDEX (export_path,'.') == 1) THEN !detected relative path, remove '.'
            export_path = export_path (2:LEN_TRIM(export_path))
            !build absolute path
            export_path = TRIM(CurrentDir() ) // TRIM(export_path)
         END IF

         !check OS convention
        IF (GetOS () == WIN32) THEN
          export_path = ReplaceChar (export_path,'/','\')
        ELSE
          export_path = ReplaceChar (export_path,'\','/')
        END IF
  
         
         !check folder exists
         IF ( .NOT. DirExists (TRIM (export_path) ) ) THEN
             CALL Catch ('info', 'Precipitation',   &
                  'creating directory:  ', argument = TRIM(export_path))
             CALL DirNew (export_path)
         END IF
     ELSE
         CALL Catch ('error', 'Precipitation',   &
                  'missing export-path')
     END IF 
     
     !starting time
     IF (KeyIsPresent ('export-start', ini, section = 'precipitation')  )  THEN
         timeString = IniReadString ('export-start', ini, 'precipitation')
         export_start = timeString
     ELSE
         CALL Catch ('error', 'Precipitation',   &
                  'missing export-start')
     END IF 
     
     !initialize timeNewExport
     timeNewExport = export_start
     
     !ending time
     IF (KeyIsPresent ('export-stop', ini, section = 'precipitation')  )  THEN
         timeString = IniReadString ('export-stop', ini, 'precipitation')
         export_stop = timeString
     ELSE
         CALL Catch ('error', 'Precipitation',   &
                  'missing export-start')
     END IF 
     
     !export dt
     IF (KeyIsPresent ('export-dt', ini, section = 'precipitation')  )  THEN
         export_dt = IniReadInt ('export-dt', ini, section = 'precipitation')
     ELSE
         CALL Catch ('error', 'Precipitation',   &
                  'missing export-dt')
     END IF 

     !coordinate reference system
     IF (KeyIsPresent ('export-epsg', ini, section = 'precipitation')  )  THEN
         export_epsg = IniReadInt ('export-epsg', ini, section = 'precipitation')
         
         exportGridMapping = DecodeEPSG (export_epsg)
         IF (exportGridMapping == precipitationRate % grid_mapping) THEN
            needConversion = .FALSE.
            !initialize grid for exporting with CRS as precipitationRate
            CALL NewGrid (exportedGrid, precipitationRate)
            CALL NewGrid (exportedGridVar, precipitationRate)
         ELSE
            needConversion = .TRUE.
            !initialize grid for converting with required CRS
            exportedGrid % grid_mapping = DecodeEPSG (export_epsg)
            exportedGridVar % grid_mapping = DecodeEPSG (export_epsg)
         END IF
     ELSE
         CALL Catch ('info', 'Precipitation',   &
                  'export-epsg not defined, use default')
         needConversion = .FALSE.
         !initialize grid for exporting with CRS as precipitationRate
         CALL NewGrid (exportedGrid, precipitationRate)
         CALL NewGrid (exportedGridVar, precipitationRate)
     END IF 

     !export file format 
     IF (KeyIsPresent ('export-format', ini, section = 'precipitation')  )  THEN
         export_format = IniReadInt ('export-format', ini, section = 'precipitation')
     ELSE
         CALL Catch ('error', 'Precipitation',   &
                  'missing export-format')
     END IF 

     IF (export_format == 3) THEN
       !precipitation map  
       CALL SetLongName ( 'precipitation_amount', exportedGrid)
       CALL SetStandardName ( 'precipitation_amount', exportedGrid)
       CALL SetUnits ('kg m-2', exportedGrid) !this unit is for exporting grid, it is converted internally to m/s
       !if file exists, remove it
       export_file = TRIM(export_path) //  'precipitation.nc'
       IF ( FileExists (export_file) ) THEN
          CALL FileDelete (export_file)
       END IF
       
       !variance of kriging 
       CALL SetLongName ( 'precipitation_amount_variance', exportedGridVar)
       CALL SetStandardName ( 'precipitation_amount_variance', exportedGridVar)
       CALL SetUnits ('kg m-2', exportedGridVar) !this unit is for exporting grid
       !if file exists, remove it
       export_file_var = TRIM(export_path) //  'precipitation_variance.nc'
       IF ( FileExists (export_file_var) ) THEN
          CALL FileDelete (export_file_var)
       END IF
       
     END IF

  END IF
	
	!complete initialization

  IF (interpolationMethod == 0) THEN
				!Get the dt of imported  field. Assume dt is regular	
				dtGrid = GetDtGrid (filename = fileGrid, checkRegular = .TRUE.)
				!check dt is multiple of dtGrid
        IF (.NOT.(MOD(dtPrecipitation,dtGrid) == 0)) THEN
            CALL Catch ('error', 'Precipitation',   &
                'dt precipitation is not multiple of dt of input grid')
        END IF
   ELSE
        !populate raingages metadata
        CALL ReadMetadata (fileunit, raingages)

        !check spatial reference system
        IF ( .NOT. raingages % mapping == mask % grid_mapping)  THEN
            CALL Catch ('info', 'Precipitation',   &
		              'converting coordinate of stations')
            !convert stations' coordinate
            point1 % system = raingages % mapping
            point2 % system = mask % grid_mapping
            raingages % mapping = mask % grid_mapping
            DO i = 1, raingages % countObs
              point1 % easting = raingages % obs (i) % xyz % easting
              point1 % northing = raingages % obs (i) % xyz % northing
              point1 % elevation = raingages % obs (i) % z
              CALL Convert (point1, point2)
              raingages % obs (i) % xyz % easting = point2 % easting
              raingages % obs (i) % xyz % northing = point2 % northing 
            END DO
        END IF
                         
        !set supplementary raingages network for elevation drift
        IF (elevationDrift == 1) THEN
           stationsRefElev =  raingages
           DO i = 1, raingages % countObs
              stationsRefElev % obs (i) % xyz % elevation = refElevation
           END DO     
        END IF       
	
  END IF
   
RETURN
END SUBROUTINE PrecipitationInit